home *** CD-ROM | disk | FTP | other *** search
- /* extras.pl:
- Extensions to MIKE. See MIKE.INI for an explanation of the
- ?- allow_prolog... declarations in this file.
-
- The following facilities are defined in this file:
- 1. Simple multiple-choice menus
- 2. A 'forall' facility
- */
-
- /* special menu handling code */
- /* next line makes 'ask_menu' legal on right hand side of MIKE rules */
-
- ?- allow_prolog_rhs(ask_menu(_,_,_)).
-
- /*
- 'ask_menu' facility (right hand side of MIKE rules only)
- ---------------------------------------------------------
- ask_menu(Object, Relation, List) displays a numbered menu of
- all the items in List and prompts the user to type in number(s).
-
- For example:
- rule a forward
- if
- diagnosing &
- [current_patient, P]
- then
- ask_menu(P,exhibits_symptom,[sneezing,coughing,headache,spots]).
-
- The end-user types in the numbers (1,2,3,4, or some combination, in
- this case) and the corresponding list elements are then stored
- in working memory as a triple: [Object, Relation, Choice]
- for each numbered Choice which was presented in the List.
- e.g. [john, exhibits_symptom, sneezing]
- An example of its use may be found in the file FLU2.KB
-
- */
-
- ask_menu(_,_,[]):- !,
- 'pd624 write'(['Error: ask menu must be called with a list of menu',nl,
- 'elements, not with an empty list',nl]).
- ask_menu(Object,Relation,List):-
- 'pd624 write'(['**********************************************',nl]),
- draw_and_read_menu(1,List,Menu),
- 'pd624 write'(['Choose the items from the menu by typing the',nl,
- 'corresponding number(s). Separate numbers with commas e.g.',nl,
- '1,3,5.',nl,
- 'REMEMBER to use a FULL STOP (''.'') at the end',nl,'==> ']),
- read(Selections),
- add_selections_to_wm(Object,Menu,Selections,Relation),
- nl.
-
- draw_and_read_menu(_,[],[]).
- draw_and_read_menu(N,[H|T],[N-H|Rest]):-
- 'pd624 write'([t/6,N,' - ',H,nl]),
- N1 is N + 1,
- draw_and_read_menu(N1,T,Rest).
-
- add_selections_to_wm(Thing,Menu,(A,B),Relation):-
- 'pd624 member'(A-Item,Menu),
- add [Thing,Relation,Item],
- add_selections_to_wm(Thing,Menu,B,Relation).
- add_selections_to_wm(Thing,Menu,(A,B),Relation):- !,
- 'pd624 write'(['Error : ',A,' is not a legal menu entry and will',nl,
- 'be ignored.',nl]),
- add_selections_to_wm(Thing,Menu,B,Relation).
- add_selections_to_wm(Thing,Menu,Num,Relation):-
- 'pd624 member'(Num-Item,Menu),
- add [Thing,Relation,Item].
- add_selections_to_wm(_,_,A,_):-
- 'pd624 write'(['Error : ',A,' is not a legal menu entry and will',nl,
- 'be ignored.',nl]).
-
- /* FORALL */
-
- /*
- 'forall' facility (for left hand side of MIKE rules only)
- -----------------------------------------------------------
- forall(Pattern1, Pattern2) tests whether all of the variables
- which match working memory within Pattern1 also match working memory
- within Pattern2. For instance, suppose working memory contains
- the following patterns:
- [john, likes, mary]
- [john, likes, sue]
- [john, likes, betty]
- [bill, likes, mary]
- [bill, likes, betty]
- [bill, likes, sue]
-
- The following rule succeeds with the above working memory:
-
- rule b forward
- if
- forall([john, likes, X], [bill, likes, X])
- then
- announce ['bill likes all the people that john likes'].
-
- If we typed in ?- remove [bill, likes, sue].
- Then the above rule b would fail
- */
-
- ?- allow_prolog_lhs(forall(_,_)).
-
- forall(Pattern1, Pattern2) :-
- setof(in_wm(Pattern2), in_wm(Pattern1), Cases),
- forall_tryall(Cases).
-
- forall_tryall([Case|Cases]) :-
- call(Case),
- forall_tryall(Cases).
-
- forall_tryall([]).